home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
prolog
/
ai.prl
/
opnprlg1.hqx
/
Open Prolog
/
Samples
/
router
< prev
next >
Wrap
Text File
|
1993-04-15
|
4KB
|
152 lines
%This code implements Lees (?) Algorithm for searching for a route on a PCB
%sample call: eraseBoard,drawCircuitBoard,drawSearch(p(9,7),p(10,15)).
:- op(10,xfy,:).
%specification of the sample board and its sample components
board(0:0-40:60). %co-ordinates as in Mac - Top:Left-Bottom:Right
%components
component(2:4-6:8).
component(8:8-13:13).
component(12:3-16:5).
component(10:16-11:28).
%setup constants for drawing
magnification(7,7).
offset(3,40).
colour(component,5). %green
%colours 0-7 below
%black,yellow,magenta,red,cyan,green,blue,white
%assume 1 unit grid
%points: p(X,Y)
%main routine
drawSearch(A,B) :-
drawPoint(A,0,5),
drawPoint(A,0,3),
drawPoint(B,0,5),
pathFind(0,[A],B,X-[0-[A]]),!,
retracePath(X,B).
pathFind(C,P,D,X-X) :-
member(D,P).
pathFind(C,Pl,D,G-[Co-Lo|H]) :-
C1 is C+1,
getMoves(Pl,L,Lo),
drawPoints(L,C1,3),!,
pathFind(C1,L,D,G-[C-Pl,Co-Lo|H]).
getMoves([],[],Ex).
getMoves([P|R],[N|X],Ex) :-
move(P,N),
not member(N,Ex),!,
getMoves([P|R],X,[N|Ex]).
getMoves([P|R],X,Ex) :-
getMoves(R,X,[P|Ex]).
move(p(X,Y),p(X1,Y)) :- X1 is X+1,legal(X1,Y).
move(p(X,Y),p(X1,Y)) :- X1 is X-1,legal(X1,Y).
move(p(X,Y),p(X,Y1)) :- Y1 is Y+1,legal(X,Y1).
move(p(X,Y),p(X,Y1)) :- Y1 is Y-1,legal(X,Y1).
legal(X,Y) :- board(T:L-B:R),X>=L,X=<R,Y>=T,Y=<B,not inComponent(X,Y).
%retrace & draw path found
retracePath([_-[X]],X).
retracePath([_-L|R],P) :-
member(C,L),move(P,C),drawLine(P,C),
retracePath(R,C).
%some drawing stuff
drawCircuitBoard :-
board(Board),
drawBoard(Board),
drawComponents.
drawComponents :-
component(Component),
drawComponent(Component),fail.
drawComponents.
drawBoard(Top:Left-Bottom:Right) :-
magnification(ByX,ByY),
offset(Xo,Yo),
T is Top*ByY+Yo,
L is Left*ByX+Xo,
B is Bottom*ByY+Yo,
R is Right*ByX+Xo,
draw(1,'The Board'(T,L,B,R),_).
eraseBoard :-
draw(2,_,_).
drawComponent(Top:Left-Bottom:Right) :-
magnification(ByX,ByY),
T is Top*ByY,
L is Left*ByX,
B is Bottom*ByY,
R is Right*ByX,
colour(component,C),
draw(9,color(C),_),
draw(4,rect(L,T,R,B),_).
drawPoint(p(X,Y),C,Size) :-
magnification(ByX,ByY),
Delta is Size/2,
T is Y*ByY-Delta,
L is X*ByX-Delta,
B is T+Size,
R is L+Size,
Cl is C mod 7,
draw(9,color(Cl),_),
draw(4,rect(L,T,R,B),_).
drawLines([p(X1,Y1),p(X2,Y2)|Rest],C) :-
!,
magnification(ByX,ByY),
T is Y1*ByY-1,
L is X1*ByX-1,
B is T+3,
R is L+3,
Cl is C mod 6,
draw(9,color(Cl),_),
draw(4,rect(L,T,R,B),_),
T2 is Y2*ByY-1,
L2 is X2*ByX-1,
B2 is T2+3,
R2 is L2+3,
Xs is L+1,Ys is T+1,
Xe is L2+1,Ye is T2+1,
draw(4,rect(L2,T2,R2,B2),_),
draw(3,line(Xs,Ys,Xe,Ye),_),
drawLines([p(X2,Y2)|Rest],C).
drawLines(_,_).
drawLine(p(X1,Y1),p(X2,Y2)) :-
magnification(ByX,ByY),
T is Y1*ByY,
L is X1*ByX,
T2 is Y2*ByY,
L2 is X2*ByX,
draw(3,line(L,T,L2,T2),_).
drawPoints([],_,_).
drawPoints([X|Y],C,S) :- drawPoint(X,C,S),drawPoints(Y,C,S).
%some utilities
inComponent(X,Y) :-component(T:L-B:R),X>=L,X=<R,Y>=T,Y=<B.
member(X,[X|_]).
member(X,[_|R]) :- member(X,R).
append([],X,X).
append([X|Y],Z,[X|R]) :- append(Y,Z,R).